DivertFlow Subroutine

public subroutine DivertFlow(time, div, Qin, Qout)

Discharge routing through diversion. Discharge is split between river and diversion channel

Arguments

Type IntentOptional Attributes Name
type(DateTime), intent(in) :: time
type(Diversion), intent(inout) :: div
real(kind=float), intent(in) :: Qin

Input discharge at time t + dt (m3/s)

real(kind=float), intent(out) :: Qout

downstream discharge at time t + dt (m3/s)


Variables

Type Visibility Attributes Name Initial
character(len=3), public :: QdivertedDOY
integer(kind=short), public :: doy

day of year


Source Code

SUBROUTINE DivertFlow &
!
( time, div, Qin, Qout)

!arguments with intent in:
TYPE(DateTime), INTENT(IN)     :: time
REAL(KIND = float), INTENT(IN) :: Qin !!Input discharge at time t + dt (m3/s)

!arguments with intent inout:
TYPE (Diversion), INTENT(INOUT) :: div

!arguments with intent out:
REAL(KIND = float), INTENT(OUT) :: Qout !!downstream discharge at time t + dt (m3/s)

!local declarations
INTEGER (KIND = short)          :: doy !!day of year
CHARACTER (LEN = 3)             :: QdivertedDOY

!-------------------------------end of declaration-----------------------------
    
!compute day of year (used to set ecological flow and weir function)
doy = DayOfYear (time, 'noleap') 

!set doy for weir function 
QdivertedDOY = ToString ( div % weirDOY (doy) )
       
CALL TableGetValue ( valueIn = Qin, tab = div % weir, keyIn = 'Qstream', &
                    keyOut = QdivertedDOY, match = 'linear', &
                    valueOut = div % QinChannel, bound = 'extendconstant' )


!check environmental flow and set Qout
div % QinChannel = MIN ( Qin - div % eFlow (doy), div % QinChannel)

IF ( div % QinChannel < 0. ) THEN !Qin is less than eflow
    div % QinChannel = 0.
END IF

!set Qout
Qout = Qin - div % QinChannel

RETURN
END SUBROUTINE DivertFlow